home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power Programmierung
/
Power-Programmierung (Tewi)(1994).iso
/
prolog
/
pdprolog
/
sqr_game.pro
< prev
next >
Wrap
Text File
|
1986-05-05
|
16KB
|
395 lines
/* ---------------------------------------------------------------------
GAME of SQUARES January 1986
George Planansky
Amethystems
11 Varnum St., Arlington, MA 02174,
617/641-3128.
This was written with A.D.A PD PROLOG V 1.6a.
(Automata Design Associates
1570 Arran Way, Dresher, PA. 19025
215/646-4894.)
INSTRUCTIONS
This game file SQR_GAME.PRO, and the interpreter file PDPROLOG.EXE, need be
in the active PC/MS -DOS directory.
Invoke the interpreter from DOS with:
> "PDPROLOG <Return>".
Tell the interpreter to load game program by entering:
?- "consult(sqr_game). <Return>"
Start squares by entering:
?-"squares. <Return>"
Note that all entries must follow the above format; thus:
?-"2. <Return>"
enters the integer "2" .
Press <Esc> to quit the game to the interpreter.
To return to DOS use: ?- "exitsys. <Return>"
To replay the game you must exit the interpreter and start over,
as retract and asserts are invoked during play.
With my system and my version of PD PROLOG, I have to restart the
computer to replay the game. I used a Zenith 151 with 640 K.
Note from Bob Morein: You can reinitialize the game, without
exiting, by using the predicate command "forget( user )". This
retracts all clauses that have been asserted by the program.
COMMENTs
There would seem to be two ideal strategems in game playing:
1) Look at: the present board position alone could be evaluated according
to some set of criteria, yielding the desired next move.
2) Play ahead: all possible lines of play could be followed, each to the
end or determining point of the game. The most favorable line of play
would then give the next move.
A limited look-ahead would use both.
While PROLOG seems naturally suited to recursive searching, this program
uses the first method. A simple choice protocol is here coded in PROLOG
using ordered facts and directed iterations to instill priorities. A line
is is chosen in accordance with two values:
1. the line is a member of a square having a certain number of entries,
or "sq-entrity" (coded as S).
2. the adjoining square via that line has a certain number of entries,
the "adj-entrity" (coded as A).
For lines in the interior of the board, which each belong to two "regular"
squares, the distinction of S vs A squares is moot. Exterior lines in this
program are deemed to all be the neighbor of a virtual exterior square, of
Id zero, and this choice of fudge makes the S/A distinction, and some other
supporting fudgework, necessary.
The nearest neighbor weighting assigned to lines in this program is not
enough by which to read board configurations, and this program loses.
Another version which also considers next-nearest neighbor effects does
better until it runs out of symbol space after about 5 moves.
As long as no one has published a "solution", it might be fun to have a PROLOG
game competition, using squares of 3 x 3 or 4 x 4 size. PDPROLOG would be
an appropriate instrument for run-offs -- it would be a further nice way of
promoting interest in the language. Something for PROLOG groups to pick up?
I would enjoy hearing suggestions on this.
* * * * * * * * * * * * * * * * * *
We played this game for a while back in high school (class of '65). I have
no idea where it came from. For all I know one of us re-invented it. The
funny thing is that we never figured out a winning strategy for a 3 x 3
board, though we were sure one existed. Geometry had given us a taste of the
power of logic, and it looked like things were going to make sense.
Newton and Hutton, Godel and God, would come later.
Maybe it was the 4 x 4 that stumped us. I hope the solution to squares
( => 3 by 3) is not painfully obvious.
My vigorous and appreciative thanks go to ADA for disseminating a nice
public domain PROLOG.
* * * * * * * * * * * * * * * * * * * *
F.W.I.W. ...
The structures square/2 and Gr:grid/12 demonstrate the two basic ways that
data and structures are stored, accessed, and manipulated in PROLOG:
1. as arguments of a predicate (grid/12), and,
2. as facts or components of facts in the database (square/5).
Notice that Gr is an argument of many of the predicates in this program,
and is passed between them by sharing.
Square/5 however is accessed by matching with the database, and, by revising
the database via retract & asserta.
You might ponder what sort of lives Gr and square/5 lead, existentially,
in this program. The discussion to card_file (see CARDFILE.PRO) touches
on this. One use of retract/asserts data is within clauses that terminate
with a cut-fail, to realize the contrary intentions of space reclamation
and data survival.
Core PROLOG, like core Pascal, doesn't offer much by way of screen control.
Here, do_show_display/1 uses available screen output predicates to display
the current game board.
Notice that do_show_display/1 receives Gr as an argument and accesses
square/5 by matching.
The characters, on screen, of the displayed board consist of constants and
variables. The variables correspond to the parts of the display that may
change from play to play, such as the lines. do_show_display/1 tests
the status of the components of Gr and of the squares to choose the
appropriate instantiations of the display variables, and passes them to
do_display/18.
There are two show_display/1 clauses so that do_show_display/1 can fail
after its screen output occurs as a side effect. On failure, tentatively
instantiated variables in the tail of a clause become de-instantiated, and
hopefully vaporize along with their trail. This is a stab at saving
memory, though I still run out of symbol space, whatever that is.
Some other items:
* The predicates play_game/2 and which_move/3 demonstrate decison/switching
behavior.
* score/5 steps its way through the facts square/5. What are the ultimate
and penultimate goals of score/5? Note the boundary case(s), and how the
scores are carried along, then delivered to the right arguments. This
is a PROLOG version of a Pascal repeat-until iteration.
* open_grid/2 is similarly iterative with more than one possible exit.
* own_up demonstrates use of retract and asserta, and generates a flag for
which_move/3. A later version of own_up uses retract and asserta on the
flag too, and has a cut-fail ending.
* I had originally used recursion (as, say, in C & M 's append) instead
of iteration (as in score/5) in some predicates, but changed to the
latter with intentions of efficiency. It may be that this is less
efficient in PDPROLOG, the way I have done it.
----------------------------------------------------------------------- */
/* sqr_game.pro V 2 (nearest neighbor entry priorities; iterations etc.
not much optimized) */
/* ------------------- board data --------------------------------*/
/* Id, Si, Ad,En,Ow Si>sides, Ad>adjacent Id's,
Ow> owner. */
square(0, [_], [_], 0, 0).
square(1, [10, 1, 2, 3], [0,2,4], 0, 1).
square(2, [ 3, 4, 5, 6], [0,1,3], 0, 2).
square(3, [ 6, 7, 8, 9], [0,2,4], 0, 3).
square(4, [ 9,11,12,10], [0,1,3], 0, 4).
/* Id = 0 is a "virtual" square for lines on the outer margins of the board.
This is a lame device to make some of the procedures work without
messy exceptions; but, messy exceptions are then required on its account */
/* line_square gives a line number and its adjoining squares. The order
of these lines affects the order of choice in choose_line */
/* L,S1,S2 */
line_square(1,1,0).
line_square(2,1,0).
line_square(3,1,2).
line_square(4,2,0).
line_square(5,2,0).
line_square(6,2,3).
line_square(7,3,0).
line_square(8,3,0).
line_square(9,3,4).
line_square(10,1,4).
line_square(11,4,0).
line_square(12,4,0).
/* ---------------------------- grid ------------------------------------*/
/* Gr = grid(G1,G2,G3,G4,G5,G6,G7,G8,G9,G10,G11,G12).
Gr records the status of the lines. Instantiated variables G#
indicate a line has been entered during play. Functor and
arg are used, mostly, instead of simply writing out grid(etc...),
to save space and to make it easier to expand the number of lines. */
is_a_grid(Gr) :- functor(Gr, grid, 12).
open_line(Gr,L) :- arg(L,Gr,V), var(V).
open_grid(Gr,13) :- !,fail.
open_grid(Gr, L) :- arg(L,Gr,V), var(V),print('\ngrid open'),!.
open_grid(Gr, L) :- Ln is L + 1, open_grid(Gr,Ln).
/* ------------------------------ play_game ------------------------------*/
/* ///me_move/// */
/* priority(entries in a line's home square, entries in its adjacent square */
priority(3,2) :- print('\nP 32 ').
priority(3,_) :- print('\nP 3* ').
priority(0,0) :- print('\nP 00 ').
priority(0,1) :- print('\nP 01 ').
priority(1,1) :- print('\nP 11 ').
priority(2,0) :- print('\nP 20 ').
priority(2,1) :- print('\nP 21 ').
priority(1,2) :- print('\nP 12 ').
priority(0,2) :- print('\nP 02 ').
priority(_,_) :- print('\nP ** ').
me_move(Gr,Next) :- print('My move ...'),
open_grid(Gr,1), print(' choosing line ...'),
priority(S,A),
choose_line(Gr,S,A,L),!, arg(L,Gr,L),
print('& entered.'),
print('\n ... check entries ... '),
own_up(L,'M',XX),!,
which_move(XX, me, Next).
me_move(Gr,over) :- print('\nI have no more moves.'),!.
choose_line(Gr,En1,En2,L) :- square(Id1,_,_,En1,_),
Id1 \= 0,
square(Id2,_,_,En2,_),
print(' ',Id1,Id2),
match(L,Id1,Id2),
open_line(Gr,L),
print('\n',L,' chosen '), !.
match(L,Id1,Id2) :- line_square(L,Id1,Id2).
match(L,Id1,Id2) :- line_square(L,Id2,Id1).
/* ////you_move//// */
you_move(Gr,Next) :- open_grid(Gr,1),
get_line(Gr,L),!,
print('\n...check entries...'),
own_up(L,'Y',XX),!, which_move(XX, you, Next),!.
you_move(Gr,over) :- print('\nYou have no more moves.'),!.
get_line(Gr,L) :- print('\nEnter the line number (1-12) of your move.>>'),
read( R), check(Gr,R,L), arg(L,Gr,L),
print('\ & entered.'),!.
get_line(Gr,L) :- print('\nillegal or unavailable entry, try again\n'),
get_line(Gr,L).
check(Gr,R,R) :- print('<',R,'>'),integer(R),
R > 0, R < 13,
arg(R,Gr,V), var(V),
print(' new entry, accepted ...').
/* ///common move/// */
own_up(L,Who,XX):- line_square(L,Id1,Id2),
owner(Id1,Who,YY),
owner(Id2,Who,ZZ),
( ((YY = xx ; ZZ = xx), XX = xx)
; (XX = xy) ),
print('... checked ').
owner(Id,Who,WW) :- Id \= 0,
square(Id,Si,Ad,En,Ow), Ena is En+1,
retract(square(Id,Si,Ad,En,Ow)),
( (Ena = 4, Owa = Who, WW = xx, print('\n',Who,' owns ',Id))
; (Owa = Ow, WW = xy) ),
asserta(square(Id,Si,Ad,Ena,Owa)).
owner(_,_,xy).
which_move(xx, This, This) :- !.
which_move(xy, me, you) :- !.
which_move(xy, you, me) :- !.
/* ///main/// */
play_game(Gr,you) :- show_display(Gr), you_move(Gr,Next),!,play_game(Gr,Next).
play_game(Gr, me) :- show_display(Gr), me_move(Gr,Next),!,play_game(Gr,Next).
play_game(Gr,over).
/* .........................end play_game................................*/
/* ---------------------- Display predicates -------------------------- */
show_display(Gr) :- do_show_display(Gr).
show_display( _).
do_show_display(Gr) :-
P = '.', V = '|', H = '-', SP = ' ', DT = '*',
Gr = grid(G1,G2,G3,G4,G5,G6,G7,G8,G9,G10,G11,G12),
( (var(G1), L1 = P) ; (L1 = V) ),
( (var(G2), L2 = P) ; (L2 = H) ),
( (var(G3), L3 = P) ; (L3 = V) ),
( (var(G4), L4 = P) ; (L4 = H) ),
( (var(G5), L5 = P) ; (L5 = V) ),
( (var(G6), L6 = P) ; (L6 = H) ),
( (var(G7), L7 = P) ; (L7 = V) ),
( (var(G8), L8 = P) ; (L8 = H) ),
( (var(G9), L9 = P) ; (L9 = V) ),
( (var(G10), L10 = P) ; (L10 = H) ),
( (var(G11), L11 = P) ; (L11 = V) ),
( (var(G12), L12 = P) ; (L12 = H) ),
square(1,_,_,_,O1), square(2,_,_,_,O2),
square(3,_,_,_,O3), square(4,_,_,_,O4),
do_display(L1,L2,L3,L4,L5,L6,L7,L8,L9,L10,L11,L12,SP,DT,O1,O2,O3,O4),
!, fail.
do_display(L1,L2,L3,L4,L5,L6,L7,L8,L9,M0,M1,M2,SP,DT,O1,O2,O3,O4) :-
nl,tab(10),
print(DT,L2,L2,L2,L2, 2,L2,L2,L2,L2,DT,L4,L4,L4,L4, 4,L4,L4,L4,L4,DT),
nl,tab(10),
print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
nl,tab(10),
print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
nl,tab(10),
print( 1,SP,SP,SP,SP,O1,SP,SP,SP,SP, 3,SP,SP,SP,SP,O2,SP,SP,SP,SP, 5),
nl,tab(10),
print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
nl,tab(10),
print(L1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L3,SP,SP,SP,SP,SP,SP,SP,SP,SP,L5),
nl,tab(10),
print(DT,M0,M0,M0, 1, 0,M0,M0,M0,M0,DT,L6,L6,L6,L6, 6,L6,L6,L6,L6,DT),
nl,tab(10),
print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
nl,tab(10),
print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
nl,tab(10),
print( 1, 1,SP,SP,SP,O4,SP,SP,SP,SP, 9,SP,SP,SP,SP,O3,SP,SP,SP,SP, 7),
nl,tab(10),
print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
nl,tab(10),
print(M1,SP,SP,SP,SP,SP,SP,SP,SP,SP,L9,SP,SP,SP,SP,SP,SP,SP,SP,SP,L7),
nl,tab(10),
print(DT,M2,M2,M2, 1, 2,M2,M2,M2,M2,DT,L8,L8,L8,L8, 8,L8,L8,L8,L8,DT),
nl,!.
/* .............................end display.............................. */
intro_squares:-
print('\nGAME of SQUARES\n\n'),
print('players: There are two players, you (a.k.a "Y") and mr (a.k.a. "M").\n'),
print('goal : The player who gains the most squares, wins.\n'),
print(' The player that completes a square will own that square.\n'),
print('board : A grid of 4 squares, corners indicated by the stars (*),\n'),
print(' sides indicated by the dotted lines.\n'),
print(' Initially all sides are blank and nonr are owned.\n'),
print('a play : A play consists of filling in a side of a square, with a line.\n'),
print('a turn : A player MUST make a play if it is his or her turn.\n'),
print(' If a play completes a square, the player MUST make a further play.\n'),
print(' If a play does not complete a square, that turn ends.\n\n'),!.
play :-
print('\nShall I start? (enter y/n): '),
( (read(y), Who = me) ; (Who = you) ),
print('\nGAME of SQUARES ... let the play begin!'),
is_a_grid(Gr),
play_game(Gr,Who), !.
/* --------------------- Scoring & Winner -------------------------- */
get_winner :- score(Y,M,0,0,1),
print('\nGame over -- the outcome is:'),
print('\n your squares> ',Y),
print('\n my squares> ',M),
nl, winner(Y,M).
score(Y, M, Y,M,5).
score(Yt,Mt,Y,M,I) :- square(I,_,_,_,'Y'), Y2 is Y+1, I2 is I+1,
score(Yt,Mt,Y2,M,I2).
score(Yt,Mt,Y,M,I) :- square(I,_,_,_,'M'), M2 is M+1, I2 is I+1,
score(Yt,Mt,Y,M2,I2).
winner(4,_) :- print('\nYou won. Ever play this game before?.').
winner(3,_) :- print('\nYou win ...\n\n how about a little bet on the side?').
winner(2,_) :- print('\nA tie. Close call, n\'est-ce pas? .').
winner(1,_) :- print('\nI win. But what did you expect?').
winner(0,_) :- print('\nI win. Pay up, sucker!').
/* .....................end scoring & winner.......................... */
/* starting clause */
squares:-
intro_squares,
play,
get_winner.
/* end of game.pro */